Initialize sediment related variables
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=300), | intent(in) | :: | iniFile |
file containing configuration information |
||
integer(kind=short), | intent(out) | :: | dtRoute |
time step for sediment routing |
||
character(len=300), | intent(out) | :: | fileOutSedimentRouting |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
character(len=300), | public | :: | filename | ||||
integer(kind=short), | public | :: | iin | ||||
type(IniList), | public | :: | iniDB |
store configuration info |
|||
integer(kind=short), | public | :: | is | ||||
integer(kind=short), | public | :: | jin | ||||
integer(kind=short), | public | :: | js | ||||
integer(kind=short), | public | :: | k |
SUBROUTINE SedimentInit & ! (iniFile, dtRoute, fileOutSedimentRouting) USE IniLib, ONLY: & !Imported routines: IniOpen, IniClose, SectionIsPresent, & KeyIsPresent, & IniReadString, IniReadInt, & !Imported type definitions: IniList USE GridOperations, ONLY: & !Imported routines GridByIni, CRSisEqual, & GridByIni USE StringManipulation, ONLY: & !Imported routines: ToString IMPLICIT NONE !Argument with intent in: CHARACTER (LEN = 300), INTENT(IN) :: iniFile !!file containing configuration information !Argument with intent out: INTEGER (KIND = short), INTENT(OUT) :: dtRoute !!time step for sediment routing CHARACTER (LEN = 300), INTENT(OUT) :: fileOutSedimentRouting !local declarations: TYPE(IniList) :: iniDB !!store configuration info CHARACTER (LEN = 300) :: filename INTEGER (KIND = short) :: k, iin, jin, is, js !------------end of declaration------------------------------------------------ CALL Catch ('info', 'Sediment', 'initialize sediment module ') !-------------------------------------------- ! open and read configuration file !-------------------------------------------- CALL IniOpen (iniFile, iniDB) !------------------------------------------- ! load parameters and options !------------------------------------------- !soil erodibility factor IF (SectionIsPresent('soil-erodibility', iniDB)) THEN CALL GridByIni (iniDB, rusleK, section = 'soil-erodibility') IF ( .NOT. CRSisEqual (mask = domain, grid = rusleK, checkCells = .TRUE.) ) THEN CALL Catch ('error', 'Sediment', & 'wrong spatial reference in soil erodibility factor' ) END IF ELSE CALL Catch ('error', 'Sediment: ', & 'missing soil-erodibility section in configuration file' ) END IF !crop and management factor IF (SectionIsPresent('crop-factor', iniDB)) THEN CALL GridByIni (iniDB, rusleC, section = 'crop-factor') IF ( .NOT. CRSisEqual (mask = domain, grid = rusleC, checkCells = .TRUE.) ) THEN CALL Catch ('error', 'Sediment', & 'wrong spatial reference in crop and management factor' ) END IF ELSE CALL Catch ('error', 'Sediment: ', & 'missing crop-factor section in configuration file' ) END IF !sediment routing IF (SectionIsPresent('route-sediment', iniDB)) THEN dtRoute = IniReadInt ('time-step', iniDB, section = 'route-sediment') IF (dtRoute > 0) THEN routeSediment = .TRUE. !read file containing cross sections to be included in output file fileOutSedimentRouting = IniReadString ('xs-output', iniDB, section = 'route-sediment') !read flow direction CALL GridByIni (iniDB, sedFlowDirection, section = 'route-sediment', & subsection = 'flow-direction' ) !read drainage network filename = IniReadString ('sediment-reach', iniDB, section = 'route-sediment') CALL ReadHydroNetwork (filename=filename, & domain = sedFlowDirection, network = sedReach) !check consistency of drainage network DO k = 1, sedReach % nreach iin = sedReach % branch(k) % i0 jin = sedReach % branch(k) % j0 DO WHILE ( .NOT.((jin == sedReach % branch(k) % j1) .AND. & (iin == sedReach % branch(k) %i1)) ) IF(domain%mat(iin,jin) == domain%nodata) THEN CALL Catch ('error', 'Sediment', & 'error in checking river drainage: ' , & argument = 'reach out of the basin row ' // & ToString(iin) // ' col ' // ToString(jin)) END IF CALL DownstreamCell (iin, jin, sedFlowDirection % mat(iin,jin), is, js) jin = JS iin = IS END DO !last cell of last reach IF (K == sedReach%nreach) THEN IF(domain%mat(iin,Jin) == domain%nodata) THEN CALL Catch ('error', 'Sediment', & 'error in checking drainage network: ' , & argument = 'reach out of the basin row ' // & ToString(iin) // ' col ' // ToString(jin)) END IF END IF END DO !initialize sediment routing grids CALL NewGrid (QinSS, domain) CALL NewGrid (QoutSS, domain) CALL NewGrid (PinSS, domain) CALL NewGrid (PoutSS, domain) CALL NewGrid (QinBL, domain) CALL NewGrid (QoutBL, domain) CALL NewGrid (PinBL, domain) CALL NewGrid (PoutBL, domain) CALL NewGrid (QoutSed, domain) ELSE routeSediment = .FALSE. END IF ELSE routeSediment = .FALSE. END IF !------------------------------------------------------- ! compute slope factor !------------------------------------------------------- !derive slope CALL DeriveSlope (dtm, slope) CALL ComputeSlopeFactor (slope) !------------------------------------------------------- ! initialize detachment rate grids !------------------------------------------------------- CALL NewGrid (interrillErosion, domain) !------------------------------------------------------- ! initialize !variation of sediment storage grid !------------------------------------------------------- !assume initial value = 0. CALL NewGrid (deltaSed, domain, 0.) !---------------------------------------------------- ! Configuration terminated. Deallocate ini database !---------------------------------------------------- CALL IniClose (iniDB) RETURN END SUBROUTINE SedimentInit